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