module Hasql.Private.Settings where

import qualified Data.ByteString as B
import qualified Data.ByteString.Builder as BB
import qualified Data.ByteString.Lazy as BL
import Hasql.Private.Prelude

-- |
-- 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

-- |
-- 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 :: ByteString
-> Word16 -> ByteString -> ByteString -> ByteString -> ByteString
settings ByteString
host Word16
port ByteString
user ByteString
password ByteString
database =
  ByteString -> ByteString
BL.toStrict forall a b. (a -> b) -> a -> b
$
    Builder -> ByteString
BB.toLazyByteString forall a b. (a -> b) -> a -> b
$
      forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$
        forall a. a -> [a] -> [a]
intersperse (Char -> Builder
BB.char7 Char
' ') forall a b. (a -> b) -> a -> b
$
          forall a. [Maybe a] -> [a]
catMaybes forall a b. (a -> b) -> a -> b
$
            [ forall a. Monoid a => a -> a -> a
mappend (String -> Builder
BB.string7 String
"host=") forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> Builder
BB.byteString
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. MonadPlus m => (a -> Bool) -> m a -> m a
mfilter (Bool -> Bool
not forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> Bool
B.null) (forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
host),
              forall a. Monoid a => a -> a -> a
mappend (String -> Builder
BB.string7 String
"port=") forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Word16 -> Builder
BB.word16Dec
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. MonadPlus m => (a -> Bool) -> m a -> m a
mfilter (forall a. Eq a => a -> a -> Bool
/= Word16
0) (forall (f :: * -> *) a. Applicative f => a -> f a
pure Word16
port),
              forall a. Monoid a => a -> a -> a
mappend (String -> Builder
BB.string7 String
"user=") forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> Builder
BB.byteString
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. MonadPlus m => (a -> Bool) -> m a -> m a
mfilter (Bool -> Bool
not forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> Bool
B.null) (forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
user),
              forall a. Monoid a => a -> a -> a
mappend (String -> Builder
BB.string7 String
"password=") forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> Builder
BB.byteString
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. MonadPlus m => (a -> Bool) -> m a -> m a
mfilter (Bool -> Bool
not forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> Bool
B.null) (forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
password),
              forall a. Monoid a => a -> a -> a
mappend (String -> Builder
BB.string7 String
"dbname=") forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> Builder
BB.byteString
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. MonadPlus m => (a -> Bool) -> m a -> m a
mfilter (Bool -> Bool
not forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> Bool
B.null) (forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
database)
            ]