Compare commits
No commits in common. "main" and "1.0.0.0" have entirely different histories.
@ -5,7 +5,6 @@
|
||||
module Database.PostgreSQL.Opium
|
||||
-- * Connection Management
|
||||
( Connection
|
||||
, ConnectionError
|
||||
, connect
|
||||
, close
|
||||
-- * Queries
|
||||
@ -41,7 +40,7 @@ import Database.PostgreSQL.LibPQ (Result)
|
||||
import qualified Data.Text.Encoding as Encoding
|
||||
import qualified Database.PostgreSQL.LibPQ as LibPQ
|
||||
|
||||
import Database.PostgreSQL.Opium.Connection (Connection, ConnectionError, connect, close, withRawConnection)
|
||||
import Database.PostgreSQL.Opium.Connection (Connection, connect, close, withRawConnection)
|
||||
import Database.PostgreSQL.Opium.Error (Error (..), ErrorPosition (..))
|
||||
import Database.PostgreSQL.Opium.FromField (FromField (..), RawField (..))
|
||||
import Database.PostgreSQL.Opium.FromRow (FromRow (..), ColumnTable)
|
||||
|
@ -1,10 +1,8 @@
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE OverloadedRecordDot #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Database.PostgreSQL.Opium.Connection
|
||||
( Connection
|
||||
, ConnectionError
|
||||
, unsafeWithRawConnection
|
||||
, withRawConnection
|
||||
, connect
|
||||
@ -12,20 +10,14 @@ module Database.PostgreSQL.Opium.Connection
|
||||
) where
|
||||
|
||||
import Control.Concurrent.MVar (MVar, newMVar, modifyMVar_, withMVar)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.Text (Text)
|
||||
import Database.PostgreSQL.LibPQ (ConnStatus (..))
|
||||
import Data.ByteString (ByteString)
|
||||
import GHC.Stack (HasCallStack)
|
||||
|
||||
import qualified Data.Text.Encoding as Encoding
|
||||
import qualified Database.PostgreSQL.LibPQ as LibPQ
|
||||
|
||||
newtype Connection = Connection
|
||||
{ rawConnection :: MVar (Maybe LibPQ.Connection)
|
||||
}
|
||||
|
||||
newtype ConnectionError = ConnectionError Text
|
||||
deriving (Show)
|
||||
}
|
||||
|
||||
withRawConnection
|
||||
:: HasCallStack
|
||||
@ -43,18 +35,11 @@ unsafeWithRawConnection f = withRawConnection $ \case
|
||||
Nothing -> error "raw connection is missing! perhaps the connection was already closed."
|
||||
Just rawConn -> f rawConn
|
||||
|
||||
connect :: Text -> IO (Either ConnectionError Connection)
|
||||
connect :: ByteString -> IO Connection
|
||||
connect connectionString = do
|
||||
-- Appending the client_encoding setting overrides any previous setting in the connection string.
|
||||
-- We set the client encoding here to make sure we can use it below for decoding connection
|
||||
-- error messages.
|
||||
rawConn <- LibPQ.connectdb $ Encoding.encodeUtf8 $ connectionString <> " client_encoding=UTF8"
|
||||
status <- LibPQ.status rawConn
|
||||
if status == ConnectionOk then
|
||||
Right . Connection <$> newMVar (Just rawConn)
|
||||
else do
|
||||
rawError <- fromMaybe "" <$> LibPQ.errorMessage rawConn
|
||||
pure $ Left $ ConnectionError $ Encoding.decodeUtf8Lenient rawError
|
||||
rawConn <- LibPQ.connectdb connectionString
|
||||
|
||||
Connection <$> newMVar (Just rawConn)
|
||||
|
||||
close :: Connection -> IO ()
|
||||
close conn = modifyMVar_ conn.rawConnection $ \case
|
||||
|
@ -20,7 +20,7 @@ name: opium
|
||||
-- PVP summary: +-+------- breaking API changes
|
||||
-- | | +----- non-breaking API additions
|
||||
-- | | | +--- code changes with no API change
|
||||
version: 1.1.0.0
|
||||
version: 1.0.0.0
|
||||
|
||||
-- A short (one-line) description of the package.
|
||||
-- synopsis:
|
||||
@ -126,7 +126,6 @@ test-suite opium-test
|
||||
base,
|
||||
opium,
|
||||
bytestring,
|
||||
containers,
|
||||
hspec,
|
||||
postgresql-libpq,
|
||||
time,
|
||||
|
@ -8,6 +8,7 @@ import Test.Hspec (Spec, SpecWith, around)
|
||||
import Text.Printf (printf)
|
||||
|
||||
import qualified Data.Text as Text
|
||||
import qualified Data.Text.Encoding as Encoding
|
||||
|
||||
import qualified Database.PostgreSQL.Opium as Opium
|
||||
|
||||
@ -19,7 +20,7 @@ setupConnection = do
|
||||
Just dbPort <- lookupEnv "DB_PORT"
|
||||
|
||||
let dsn = printf "host=localhost user=%s password=%s dbname=%s port=%s" dbUser dbPass dbName dbPort
|
||||
Right conn <- Opium.connect $ Text.pack dsn
|
||||
conn <- Opium.connect $ Encoding.encodeUtf8 $ Text.pack dsn
|
||||
|
||||
Right _ <- Opium.execute_ "DROP TABLE IF EXISTS person" conn
|
||||
Right _ <- Opium.execute_ "CREATE TABLE person (name TEXT NOT NULL, age INT NOT NULL, score DOUBLE PRECISION NOT NULL, motto TEXT)" conn
|
||||
|
Loading…
x
Reference in New Issue
Block a user