module Hasql.Connection.Config.ConnectionString where import Data.ByteString qualified as B import Data.Map.Strict qualified as Map import Data.Text.Encoding qualified import Hasql.Connection.Config.ConnectionString.Params qualified as Params import Hasql.Prelude type ConnectionString = ByteString class Constructs a where construct :: a -> ConnectionString fromText :: Text -> ConnectionString fromText :: Text -> ByteString fromText = Text -> ByteString Data.Text.Encoding.encodeUtf8 fromParams :: Params.Params -> ConnectionString fromParams :: Params -> ByteString fromParams = ByteString -> [ByteString] -> ByteString B.intercalate ByteString " " ([ByteString] -> ByteString) -> (Params -> [ByteString]) -> Params -> ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . ((ByteString, ByteString) -> ByteString) -> [(ByteString, ByteString)] -> [ByteString] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (ByteString, ByteString) -> ByteString forall {a}. (Monoid a, IsString a) => (a, a) -> a renderParam ([(ByteString, ByteString)] -> [ByteString]) -> (Params -> [(ByteString, ByteString)]) -> Params -> [ByteString] forall b c a. (b -> c) -> (a -> b) -> a -> c forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Params -> [(ByteString, ByteString)] forall k a. Map k a -> [(k, a)] Map.toList where renderParam :: (a, a) -> a renderParam (a k, a v) = [a] -> a forall a. Monoid a => [a] -> a mconcat [a k, a "=", a v]