mirror of
https://github.com/nikita-volkov/hasql.git
synced 2024-12-26 12:01:35 +03:00
Simplify Settings
This commit is contained in:
parent
8dde5b3864
commit
ed23377f2e
@ -12,7 +12,7 @@ main =
|
||||
H.connect settings >>= either (fail . show) use
|
||||
where
|
||||
settings =
|
||||
H.ParametricSettings host port user password database
|
||||
H.settings host port user password database
|
||||
where
|
||||
host = "localhost"
|
||||
port = 5432
|
||||
|
@ -4,9 +4,11 @@
|
||||
-- The API is completely disinfected from exceptions. All error-reporting is explicit and is presented using the 'Either' type.
|
||||
module Hasql
|
||||
(
|
||||
-- * Connection settings
|
||||
Settings.Settings(..),
|
||||
Settings.settings,
|
||||
-- * Connection
|
||||
Connection,
|
||||
Settings.Settings(..),
|
||||
ConnectionError(..),
|
||||
connect,
|
||||
disconnect,
|
||||
|
@ -10,14 +10,13 @@ import qualified Hasql.PreparedStatementRegistry as PreparedStatementRegistry
|
||||
import qualified Hasql.Decoding.Result as ResultDecoding
|
||||
import qualified Hasql.Decoding.Results as ResultsDecoding
|
||||
import qualified Hasql.Encoding.Params as ParamsEncoding
|
||||
import qualified Hasql.Settings as Settings
|
||||
import qualified Data.DList as DList
|
||||
|
||||
|
||||
{-# INLINE acquireConnection #-}
|
||||
acquireConnection :: Settings.Settings -> IO LibPQ.Connection
|
||||
acquireConnection settings =
|
||||
LibPQ.connectdb (Settings.asBytes settings)
|
||||
acquireConnection :: ByteString -> IO LibPQ.Connection
|
||||
acquireConnection =
|
||||
LibPQ.connectdb
|
||||
|
||||
{-# INLINE acquirePreparedStatementRegistry #-}
|
||||
acquirePreparedStatementRegistry :: IO PreparedStatementRegistry.PreparedStatementRegistry
|
||||
|
@ -7,40 +7,33 @@ import qualified Data.ByteString.Lazy.Builder.ASCII as BB
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
|
||||
|
||||
|
||||
-- |
|
||||
-- All settings encoded in a single byte-string according to
|
||||
-- <http://www.postgresql.org/docs/9.4/static/libpq-connect.html#LIBPQ-CONNSTRING the PostgreSQL format>.
|
||||
type Settings =
|
||||
ByteString
|
||||
|
||||
-- |
|
||||
-- Connection settings.
|
||||
data Settings =
|
||||
-- |
|
||||
-- A host, a port, a user, a password and a database.
|
||||
ParametricSettings !ByteString !Word16 !ByteString !ByteString !ByteString |
|
||||
-- |
|
||||
-- All settings encoded in a single byte string according to
|
||||
-- <http://www.postgresql.org/docs/9.4/static/libpq-connect.html#LIBPQ-CONNSTRING the PostgreSQL format>.
|
||||
RawSettings !ByteString
|
||||
deriving (Show)
|
||||
|
||||
{-# INLINE asBytes #-}
|
||||
asBytes :: Settings -> ByteString
|
||||
asBytes =
|
||||
\case
|
||||
ParametricSettings host port user password database ->
|
||||
BL.toStrict $ BB.toLazyByteString $ mconcat $ intersperse (BB.char7 ' ') $ catMaybes $
|
||||
[
|
||||
mappend (BB.string7 "host=") . BB.byteString <$>
|
||||
mfilter (not . B.null) (pure host)
|
||||
,
|
||||
mappend (BB.string7 "port=") . BB.word16Dec <$>
|
||||
mfilter (/= 0) (pure port)
|
||||
,
|
||||
mappend (BB.string7 "user=") . BB.byteString <$>
|
||||
mfilter (not . B.null) (pure user)
|
||||
,
|
||||
mappend (BB.string7 "password=") . BB.byteString <$>
|
||||
mfilter (not . B.null) (pure password)
|
||||
,
|
||||
mappend (BB.string7 "dbname=") . BB.byteString <$>
|
||||
mfilter (not . B.null) (pure database)
|
||||
]
|
||||
RawSettings bytes ->
|
||||
bytes
|
||||
-- Encode a host, a port, a user, a password and a database into the PostgreSQL settings byte-string.
|
||||
{-# INLINE settings #-}
|
||||
settings :: ByteString -> Word16 -> ByteString -> ByteString -> ByteString -> Settings
|
||||
settings host port user password database =
|
||||
BL.toStrict $ BB.toLazyByteString $ mconcat $ intersperse (BB.char7 ' ') $ catMaybes $
|
||||
[
|
||||
mappend (BB.string7 "host=") . BB.byteString <$>
|
||||
mfilter (not . B.null) (pure host)
|
||||
,
|
||||
mappend (BB.string7 "port=") . BB.word16Dec <$>
|
||||
mfilter (/= 0) (pure port)
|
||||
,
|
||||
mappend (BB.string7 "user=") . BB.byteString <$>
|
||||
mfilter (not . B.null) (pure user)
|
||||
,
|
||||
mappend (BB.string7 "password=") . BB.byteString <$>
|
||||
mfilter (not . B.null) (pure password)
|
||||
,
|
||||
mappend (BB.string7 "dbname=") . BB.byteString <$>
|
||||
mfilter (not . B.null) (pure database)
|
||||
]
|
||||
|
||||
|
@ -23,7 +23,7 @@ session (Session impl) =
|
||||
EitherT $ fmap (mapLeft ConnectionError) $ H.connect settings
|
||||
where
|
||||
settings =
|
||||
H.ParametricSettings host port user password database
|
||||
H.settings host port user password database
|
||||
where
|
||||
host = "localhost"
|
||||
port = 5432
|
||||
|
Loading…
Reference in New Issue
Block a user