2018-12-16 17:35:58 +00:00
|
|
|
module Database.PostgreSQL
|
|
|
|
( module Row
|
|
|
|
, module Value
|
|
|
|
, PGError(..)
|
|
|
|
, PGErrorDetail
|
|
|
|
, Database
|
|
|
|
, PoolConfiguration
|
|
|
|
, Pool
|
|
|
|
, Connection
|
2019-12-22 11:51:22 +00:00
|
|
|
, ConnectResult
|
2018-12-16 17:35:58 +00:00
|
|
|
, Query(..)
|
|
|
|
, newPool
|
2019-12-22 11:48:48 +00:00
|
|
|
, connect
|
2018-12-16 17:35:58 +00:00
|
|
|
, withConnection
|
|
|
|
, withTransaction
|
|
|
|
, defaultPoolConfiguration
|
|
|
|
, command
|
|
|
|
, execute
|
|
|
|
, query
|
|
|
|
, scalar
|
|
|
|
) where
|
2016-12-22 18:12:38 +00:00
|
|
|
|
2017-12-04 21:43:36 +00:00
|
|
|
import Prelude
|
|
|
|
|
2018-12-16 17:35:58 +00:00
|
|
|
import Control.Monad.Error.Class (catchError, throwError)
|
2017-06-03 11:10:15 +00:00
|
|
|
import Data.Array (head)
|
2018-12-09 20:50:13 +00:00
|
|
|
import Data.Bifunctor (lmap)
|
|
|
|
import Data.Either (Either(..), either, hush)
|
2018-11-16 11:40:30 +00:00
|
|
|
import Data.Generic.Rep (class Generic)
|
|
|
|
import Data.Generic.Rep.Show (genericShow)
|
|
|
|
import Data.Maybe (Maybe(..), maybe)
|
2016-12-22 19:25:17 +00:00
|
|
|
import Data.Newtype (class Newtype)
|
2018-11-16 11:40:30 +00:00
|
|
|
import Data.Nullable (Nullable, toMaybe, toNullable)
|
|
|
|
import Data.String (Pattern(..))
|
|
|
|
import Data.String as String
|
2018-12-16 17:35:58 +00:00
|
|
|
import Data.Traversable (traverse)
|
2018-07-15 17:51:17 +00:00
|
|
|
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
|
2018-10-21 01:24:58 +00:00
|
|
|
import Database.PostgreSQL.Row (class FromSQLRow, class ToSQLRow, Row0(..), Row1(..), fromSQLRow, toSQLRow)
|
2017-06-03 11:10:15 +00:00
|
|
|
import Database.PostgreSQL.Value (class FromSQLValue)
|
2018-07-15 17:51:17 +00:00
|
|
|
import Database.PostgreSQL.Value (class FromSQLValue, class ToSQLValue, fromSQLValue, instantFromString, instantToString, null, toSQLValue, unsafeIsBuffer) as Value
|
2018-10-21 01:24:58 +00:00
|
|
|
import Effect (Effect)
|
|
|
|
import Effect.Aff (Aff, bracket)
|
|
|
|
import Effect.Aff.Compat (EffectFnAff, fromEffectFnAff)
|
|
|
|
import Effect.Class (liftEffect)
|
2018-11-16 11:40:30 +00:00
|
|
|
import Effect.Exception (Error)
|
2018-10-21 01:24:58 +00:00
|
|
|
import Foreign (Foreign)
|
2016-12-22 18:12:38 +00:00
|
|
|
|
2018-10-21 01:24:58 +00:00
|
|
|
type Database = String
|
2016-12-22 18:12:38 +00:00
|
|
|
|
2016-12-24 12:38:36 +00:00
|
|
|
-- | PostgreSQL connection pool configuration.
|
2016-12-22 18:12:38 +00:00
|
|
|
type PoolConfiguration =
|
2018-10-21 01:24:58 +00:00
|
|
|
{ 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
|
2016-12-22 18:12:38 +00:00
|
|
|
}
|
|
|
|
|
2016-12-24 12:38:36 +00:00
|
|
|
-- | PostgreSQL connection pool.
|
2017-04-20 08:05:17 +00:00
|
|
|
foreign import data Pool :: Type
|
2016-12-22 18:12:38 +00:00
|
|
|
|
2016-12-24 12:38:36 +00:00
|
|
|
-- | PostgreSQL connection.
|
2017-04-20 08:05:17 +00:00
|
|
|
foreign import data Connection :: Type
|
2016-12-22 18:12:38 +00:00
|
|
|
|
2016-12-24 12:38:36 +00:00
|
|
|
-- | PostgreSQL query with parameter (`$1`, `$2`, …) and return types.
|
2016-12-22 19:25:17 +00:00
|
|
|
newtype Query i o = Query String
|
|
|
|
|
|
|
|
derive instance newtypeQuery :: Newtype (Query i o) _
|
|
|
|
|
2016-12-24 12:38:36 +00:00
|
|
|
-- | Create a new connection pool.
|
2018-12-06 19:08:48 +00:00
|
|
|
newPool :: PoolConfiguration -> Effect Pool
|
2018-10-21 01:24:58 +00:00
|
|
|
newPool cfg =
|
2018-12-06 19:08:48 +00:00
|
|
|
ffiNewPool $ cfg'
|
2018-11-30 06:35:29 +00:00
|
|
|
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
|
|
|
|
}
|
2018-10-21 01:24:58 +00:00
|
|
|
|
|
|
|
-- | 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
|
|
|
|
}
|
2017-06-03 11:43:30 +00:00
|
|
|
|
|
|
|
foreign import ffiNewPool
|
2018-10-21 01:24:58 +00:00
|
|
|
:: PoolConfiguration'
|
2018-07-15 17:51:17 +00:00
|
|
|
-> Effect Pool
|
2016-12-22 18:12:38 +00:00
|
|
|
|
2017-12-05 21:12:01 +00:00
|
|
|
-- | Run an action with a connection. The connection is released to the pool
|
|
|
|
-- | when the action returns.
|
2017-06-03 11:43:30 +00:00
|
|
|
withConnection
|
2018-12-09 20:50:13 +00:00
|
|
|
:: forall a
|
2016-12-22 18:12:38 +00:00
|
|
|
. Pool
|
2018-12-09 20:50:13 +00:00
|
|
|
-> (Either PGError Connection -> Aff a)
|
|
|
|
-> Aff a
|
2017-06-03 11:43:30 +00:00
|
|
|
withConnection p k =
|
2018-12-09 20:50:13 +00:00
|
|
|
bracket (connect p) cleanup run
|
2018-11-16 11:40:30 +00:00
|
|
|
where
|
2018-11-30 06:35:29 +00:00
|
|
|
cleanup (Left _) = pure unit
|
|
|
|
cleanup (Right { done }) = liftEffect done
|
2018-11-16 11:40:30 +00:00
|
|
|
|
2018-12-09 20:50:13 +00:00
|
|
|
run (Left err) = k (Left err)
|
|
|
|
run (Right { connection }) = k (Right connection)
|
2017-06-03 11:43:30 +00:00
|
|
|
|
2017-12-04 21:43:36 +00:00
|
|
|
connect
|
2018-07-15 17:51:17 +00:00
|
|
|
:: Pool
|
2018-11-16 11:40:30 +00:00
|
|
|
-> Aff (Either PGError ConnectResult)
|
|
|
|
connect =
|
|
|
|
fromEffectFnAff
|
|
|
|
<<< ffiConnect
|
|
|
|
{ nullableLeft: toNullable <<< map Left <<< convertError
|
|
|
|
, right: Right
|
|
|
|
}
|
|
|
|
|
|
|
|
type ConnectResult =
|
|
|
|
{ connection :: Connection
|
|
|
|
, done :: Effect Unit
|
|
|
|
}
|
2017-12-04 21:43:36 +00:00
|
|
|
|
|
|
|
foreign import ffiConnect
|
2018-12-09 20:50:13 +00:00
|
|
|
:: forall a
|
2018-11-16 11:40:30 +00:00
|
|
|
. { nullableLeft :: Error -> Nullable (Either PGError ConnectResult)
|
|
|
|
, right :: a -> Either PGError ConnectResult
|
|
|
|
}
|
|
|
|
-> Pool
|
|
|
|
-> EffectFnAff (Either PGError ConnectResult)
|
2017-12-04 21:43:36 +00:00
|
|
|
|
2018-12-16 17:35:58 +00:00
|
|
|
-- | Run an action within a transaction. The transaction is committed if the
|
|
|
|
-- | action returns cleanly, and rolled back if the action throws (either a
|
|
|
|
-- | `PGError` or a JavaScript exception in the Aff context). If you want to
|
|
|
|
-- | change the transaction mode, issue a separate `SET TRANSACTION` statement
|
|
|
|
-- | within the transaction.
|
|
|
|
withTransaction
|
|
|
|
:: forall a
|
|
|
|
. Connection
|
|
|
|
-> Aff a
|
|
|
|
-> Aff (Either PGError a)
|
|
|
|
withTransaction conn action =
|
|
|
|
begin >>= case _ of
|
|
|
|
Nothing → do
|
|
|
|
a ← action `catchError` \jsErr → do
|
|
|
|
void $ rollback
|
|
|
|
throwError jsErr
|
|
|
|
commit >>= case _ of
|
|
|
|
Just pgError → pure (Left pgError)
|
|
|
|
Nothing → pure (Right a)
|
|
|
|
Just pgError → pure (Left pgError)
|
|
|
|
where
|
|
|
|
begin = execute conn (Query "BEGIN TRANSACTION") Row0
|
|
|
|
commit = execute conn (Query "COMMIT TRANSACTION") Row0
|
|
|
|
rollback = execute conn (Query "ROLLBACK TRANSACTION") Row0
|
2016-12-22 18:12:38 +00:00
|
|
|
|
2016-12-24 12:38:36 +00:00
|
|
|
-- | Execute a PostgreSQL query and discard its results.
|
2016-12-22 18:12:38 +00:00
|
|
|
execute
|
2018-12-09 20:50:13 +00:00
|
|
|
:: forall i o
|
2016-12-22 18:12:38 +00:00
|
|
|
. (ToSQLRow i)
|
|
|
|
=> Connection
|
2016-12-22 19:25:17 +00:00
|
|
|
-> Query i o
|
2016-12-22 18:12:38 +00:00
|
|
|
-> i
|
2018-12-09 20:50:13 +00:00
|
|
|
-> Aff (Maybe PGError)
|
2016-12-22 19:25:17 +00:00
|
|
|
execute conn (Query sql) values =
|
2018-12-09 20:50:13 +00:00
|
|
|
hush <<< either Right Left <$> unsafeQuery conn sql (toSQLRow values)
|
2016-12-22 18:12:38 +00:00
|
|
|
|
2016-12-24 12:38:36 +00:00
|
|
|
-- | Execute a PostgreSQL query and return its results.
|
2016-12-22 18:12:38 +00:00
|
|
|
query
|
2018-12-09 20:50:13 +00:00
|
|
|
:: forall i o
|
2017-04-20 08:05:17 +00:00
|
|
|
. ToSQLRow i
|
|
|
|
=> FromSQLRow o
|
2016-12-22 18:12:38 +00:00
|
|
|
=> Connection
|
2016-12-22 19:25:17 +00:00
|
|
|
-> Query i o
|
2016-12-22 18:12:38 +00:00
|
|
|
-> i
|
2018-12-09 20:50:13 +00:00
|
|
|
-> Aff (Either PGError (Array o))
|
2018-11-16 11:40:30 +00:00
|
|
|
query conn (Query sql) values = do
|
2018-12-09 20:50:13 +00:00
|
|
|
r <- unsafeQuery conn sql (toSQLRow values)
|
|
|
|
pure $ r >>= _.rows >>> traverse (fromSQLRow >>> lmap ConversionError)
|
2016-12-22 18:12:38 +00:00
|
|
|
|
2017-06-03 11:43:30 +00:00
|
|
|
-- | Execute a PostgreSQL query and return the first field of the first row in
|
|
|
|
-- | the result.
|
2017-01-12 16:12:59 +00:00
|
|
|
scalar
|
2018-12-09 20:50:13 +00:00
|
|
|
:: forall i o
|
2017-04-20 08:05:17 +00:00
|
|
|
. ToSQLRow i
|
|
|
|
=> FromSQLValue o
|
2017-01-12 16:12:59 +00:00
|
|
|
=> Connection
|
2017-06-03 11:10:15 +00:00
|
|
|
-> Query i (Row1 o)
|
2017-01-12 16:12:59 +00:00
|
|
|
-> i
|
2018-12-09 20:50:13 +00:00
|
|
|
-> Aff (Either PGError (Maybe o))
|
2017-01-12 16:12:59 +00:00
|
|
|
scalar conn sql values =
|
2018-12-09 20:50:13 +00:00
|
|
|
query conn sql values <#> map (head >>> map (case _ of Row1 a -> a))
|
2017-01-12 16:12:59 +00:00
|
|
|
|
2018-10-09 06:30:12 +00:00
|
|
|
-- | Execute a PostgreSQL query and return its command tag value
|
|
|
|
-- | (how many rows were affected by the query). This may be useful
|
2018-11-19 06:25:59 +00:00
|
|
|
-- | for example with `DELETE` or `UPDATE` queries.
|
2018-10-08 19:06:41 +00:00
|
|
|
command
|
2018-12-09 20:50:13 +00:00
|
|
|
:: forall i
|
2018-10-08 19:06:41 +00:00
|
|
|
. ToSQLRow i
|
|
|
|
=> Connection
|
|
|
|
-> Query i Int
|
|
|
|
-> i
|
2018-12-09 20:50:13 +00:00
|
|
|
-> Aff (Either PGError Int)
|
2018-11-30 06:35:29 +00:00
|
|
|
command conn (Query sql) values =
|
2018-12-09 20:50:13 +00:00
|
|
|
map _.rowCount <$> unsafeQuery conn sql (toSQLRow values)
|
2018-10-08 19:06:41 +00:00
|
|
|
|
2018-11-30 06:35:29 +00:00
|
|
|
type QueryResult =
|
|
|
|
{ rows :: Array (Array Foreign)
|
|
|
|
, rowCount :: Int
|
|
|
|
}
|
2018-11-16 11:40:30 +00:00
|
|
|
|
|
|
|
unsafeQuery
|
2018-11-30 06:35:29 +00:00
|
|
|
:: Connection
|
2018-10-08 19:06:41 +00:00
|
|
|
-> String
|
|
|
|
-> Array Foreign
|
2018-12-09 20:50:13 +00:00
|
|
|
-> Aff (Either PGError QueryResult)
|
2018-11-30 06:35:29 +00:00
|
|
|
unsafeQuery c s =
|
2018-12-09 20:50:13 +00:00
|
|
|
fromEffectFnAff <<< ffiUnsafeQuery p c s
|
2018-11-30 06:35:29 +00:00
|
|
|
where
|
2018-11-16 11:40:30 +00:00
|
|
|
p =
|
2018-11-30 06:35:29 +00:00
|
|
|
{ nullableLeft: toNullable <<< map Left <<< convertError
|
|
|
|
, right: Right
|
|
|
|
}
|
2018-10-08 19:06:41 +00:00
|
|
|
|
2018-11-16 11:40:30 +00:00
|
|
|
foreign import ffiUnsafeQuery
|
2018-11-30 06:35:29 +00:00
|
|
|
:: { nullableLeft :: Error -> Nullable (Either PGError QueryResult)
|
2018-11-16 11:40:30 +00:00
|
|
|
, right :: QueryResult -> Either PGError QueryResult
|
|
|
|
}
|
|
|
|
-> Connection
|
2018-10-08 19:06:41 +00:00
|
|
|
-> String
|
|
|
|
-> Array Foreign
|
2018-11-30 06:35:29 +00:00
|
|
|
-> EffectFnAff (Either PGError QueryResult)
|
2018-11-16 11:40:30 +00:00
|
|
|
|
|
|
|
data PGError
|
2018-11-30 06:35:29 +00:00
|
|
|
= ConnectionError String
|
|
|
|
| ConversionError String
|
|
|
|
| InternalError PGErrorDetail
|
|
|
|
| OperationalError PGErrorDetail
|
|
|
|
| ProgrammingError PGErrorDetail
|
|
|
|
| IntegrityError PGErrorDetail
|
|
|
|
| DataError PGErrorDetail
|
|
|
|
| NotSupportedError PGErrorDetail
|
|
|
|
| QueryCanceledError PGErrorDetail
|
|
|
|
| TransactionRollbackError PGErrorDetail
|
2018-11-16 11:40:30 +00:00
|
|
|
|
|
|
|
derive instance eqPGError :: Eq PGError
|
|
|
|
derive instance genericPGError :: Generic PGError _
|
|
|
|
|
|
|
|
instance showPGError :: Show PGError where
|
2018-11-30 06:35:29 +00:00
|
|
|
show = genericShow
|
2018-11-16 11:40:30 +00:00
|
|
|
|
|
|
|
type PGErrorDetail =
|
2018-11-30 06:35:29 +00:00
|
|
|
{ severity :: String
|
|
|
|
, code :: String
|
|
|
|
, message :: String
|
|
|
|
, detail :: String
|
|
|
|
, hint :: String
|
|
|
|
, position :: String
|
|
|
|
, internalPosition :: String
|
|
|
|
, internalQuery :: String
|
|
|
|
, where_ :: String
|
|
|
|
, schema :: String
|
|
|
|
, table :: String
|
|
|
|
, column :: String
|
|
|
|
, dataType :: String
|
|
|
|
, constraint :: String
|
|
|
|
, file :: String
|
|
|
|
, line :: String
|
|
|
|
, routine :: String
|
|
|
|
}
|
2018-11-16 11:40:30 +00:00
|
|
|
|
|
|
|
foreign import ffiSQLState :: Error -> Nullable String
|
|
|
|
foreign import ffiErrorDetail :: Error -> PGErrorDetail
|
|
|
|
|
|
|
|
convertError :: Error -> Maybe PGError
|
|
|
|
convertError err =
|
|
|
|
case toMaybe $ ffiSQLState err of
|
|
|
|
Nothing -> Nothing
|
|
|
|
Just sqlState -> Just $ convert sqlState $ ffiErrorDetail err
|
|
|
|
|
|
|
|
where
|
|
|
|
convert :: String -> PGErrorDetail -> PGError
|
|
|
|
convert s =
|
|
|
|
if prefix "0A" s then NotSupportedError
|
|
|
|
else if prefix "20" s || prefix "21" s then ProgrammingError
|
|
|
|
else if prefix "22" s then DataError
|
|
|
|
else if prefix "23" s then IntegrityError
|
|
|
|
else if prefix "24" s || prefix "25" s then InternalError
|
|
|
|
else if prefix "26" s || prefix "27" s || prefix "28" s then OperationalError
|
|
|
|
else if prefix "2B" s || prefix "2D" s || prefix "2F" s then InternalError
|
|
|
|
else if prefix "34" s then OperationalError
|
|
|
|
else if prefix "38" s || prefix "39" s || prefix "3B" s then InternalError
|
|
|
|
else if prefix "3D" s || prefix "3F" s then ProgrammingError
|
|
|
|
else if prefix "40" s then TransactionRollbackError
|
|
|
|
else if prefix "42" s || prefix "44" s then ProgrammingError
|
|
|
|
else if s == "57014" then QueryCanceledError
|
|
|
|
else if prefix "5" s then OperationalError
|
|
|
|
else if prefix "F" s then InternalError
|
|
|
|
else if prefix "H" s then OperationalError
|
|
|
|
else if prefix "P" s then InternalError
|
|
|
|
else if prefix "X" s then InternalError
|
|
|
|
else const $ ConnectionError s
|
|
|
|
|
|
|
|
prefix :: String -> String -> Boolean
|
|
|
|
prefix p =
|
|
|
|
maybe false (_ == 0) <<< String.indexOf (Pattern p)
|
|
|
|
|
2018-12-09 20:50:13 +00:00
|
|
|
-- onIntegrityError :: forall a. PG a -> PG a -> PG a
|
|
|
|
-- onIntegrityError errorResult db =
|
|
|
|
-- catchError db handleError
|
|
|
|
-- where
|
|
|
|
-- handleError e =
|
|
|
|
-- case e of
|
|
|
|
-- IntegrityError _ -> errorResult
|
|
|
|
-- _ -> throwError e
|