Skip to content

Commit

Permalink
make a start to stetting up hasql with db pools
Browse files Browse the repository at this point in the history
  • Loading branch information
Cmdv committed Feb 6, 2025
1 parent 8a3433f commit 53035ee
Show file tree
Hide file tree
Showing 10 changed files with 98 additions and 54 deletions.
4 changes: 2 additions & 2 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,8 @@ repository cardano-haskell-packages
d4a35cd3121aa00d18544bb0ac01c3e1691d618f462c46129271bccf39f7e8ee

index-state:
, hackage.haskell.org 2024-10-10T00:52:24Z
, cardano-haskell-packages 2024-11-26T16:00:26Z
, hackage.haskell.org 2025-02-05T12:01:20Z
, cardano-haskell-packages 2025-02-04T11:56:25Z

packages:
cardano-db
Expand Down
2 changes: 2 additions & 0 deletions cardano-db-sync/cardano-db-sync.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -189,6 +189,8 @@ library
, extra
, filepath
, groups
, hasql
, hasql-pool
, http-client
, http-client-tls
, http-types
Expand Down
15 changes: 8 additions & 7 deletions cardano-db-sync/src/Cardano/DbSync.hs
Original file line number Diff line number Diff line change
Expand Up @@ -170,19 +170,20 @@ runSyncNode metricsSetters trce iomgr dbConnString ranMigrations runMigrationFnc
logInfo trce $ "Using alonzo genesis file from: " <> (show . unGenesisFile $ dncAlonzoGenesisFile syncNodeConfigFromFile)

let useLedger = shouldUseLedger (sioLedger $ dncInsertOptions syncNodeConfigFromFile)

Db.runIohkLogging trce $
withPostgresqlConn dbConnString $
\backend -> liftIO $ do
cPool <- createPool dbConnString
bracket
cPool
Pool.release
(\pool -> do
runOrThrowIO $ runExceptT $ do
genCfg <- readCardanoGenesisConfig syncNodeConfigFromFile
isJsonbInSchema <- queryIsJsonbInSchema backend
isJsonbInSchema <- queryIsJsonbInSchema pool
logProtocolMagicId trce $ genesisProtocolMagicId genCfg
syncEnv <-
ExceptT $
mkSyncEnvFromConfig
trce
backend
pool
dbConnString
syncOptions
genCfg
Expand All @@ -203,7 +204,7 @@ runSyncNode metricsSetters trce iomgr dbConnString ranMigrations runMigrationFnc
liftIO $ runExtraMigrationsMaybe syncEnv
unless useLedger $ liftIO $ do
logInfo trce "Migrating to a no ledger schema"
Db.noLedgerMigrations backend trce
Db.noLedgerMigrations pool trce
insertValidateGenesisDist syncEnv (dncNetworkName syncNodeConfigFromFile) genCfg (useShelleyInit syncNodeConfigFromFile)

-- communication channel between datalayer thread and chainsync-client thread
Expand Down
12 changes: 6 additions & 6 deletions cardano-db-sync/src/Cardano/DbSync/Api.hs
Original file line number Diff line number Diff line change
Expand Up @@ -334,7 +334,7 @@ getCurrentTipBlockNo env = do

mkSyncEnv ::
Trace IO Text ->
SqlBackend ->
Pool ->
ConnectionString ->
SyncOptions ->
ProtocolInfo CardanoBlock ->
Expand All @@ -346,7 +346,7 @@ mkSyncEnv ::
Bool ->
RunMigration ->
IO SyncEnv
mkSyncEnv trce backend connectionString syncOptions protoInfo nw nwMagic systemStart syncNodeConfigFromFile syncNP ranMigrations runMigrationFnc = do
mkSyncEnv trce dbPool connectionString syncOptions protoInfo nw nwMagic systemStart syncNodeConfigFromFile syncNP ranMigrations runMigrationFnc = do
dbCNamesVar <- newTVarIO =<< dbConstraintNamesExists backend
cache <-
if soptCache syncOptions
Expand Down Expand Up @@ -394,7 +394,7 @@ mkSyncEnv trce backend connectionString syncOptions protoInfo nw nwMagic systemS

pure $
SyncEnv
{ envBackend = backend
{ envPool = dbPool
, envBootstrap = bootstrapVar
, envCache = cache
, envConnectionString = connectionString
Expand All @@ -421,7 +421,7 @@ mkSyncEnv trce backend connectionString syncOptions protoInfo nw nwMagic systemS

mkSyncEnvFromConfig ::
Trace IO Text ->
SqlBackend ->
Pool ->
ConnectionString ->
SyncOptions ->
GenesisConfig ->
Expand All @@ -432,7 +432,7 @@ mkSyncEnvFromConfig ::
-- | run migration function
RunMigration ->
IO (Either SyncNodeError SyncEnv)
mkSyncEnvFromConfig trce backend connectionString syncOptions genCfg syncNodeConfigFromFile syncNodeParams ranMigration runMigrationFnc =
mkSyncEnvFromConfig trce dbPool connectionString syncOptions genCfg syncNodeConfigFromFile syncNodeParams ranMigration runMigrationFnc =
case genCfg of
GenesisCardano _ bCfg sCfg _ _
| unProtocolMagicId (Byron.configProtocolMagicId bCfg) /= Shelley.sgNetworkMagic (scConfig sCfg) ->
Expand All @@ -459,7 +459,7 @@ mkSyncEnvFromConfig trce backend connectionString syncOptions genCfg syncNodeCon
Right
<$> mkSyncEnv
trce
backend
dbPool
connectionString
syncOptions
(fst $ mkProtocolInfoCardano genCfg [])
Expand Down
3 changes: 1 addition & 2 deletions cardano-db-sync/src/Cardano/DbSync/Api/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,12 +33,11 @@ import Control.Concurrent.Class.MonadSTM.Strict.TBQueue (StrictTBQueue)
import qualified Data.Strict.Maybe as Strict
import Data.Time.Clock (UTCTime)
import Database.Persist.Postgresql (ConnectionString)
import Database.Persist.Sql (SqlBackend)
import Ouroboros.Consensus.BlockchainTime.WallClock.Types (SystemStart (..))
import Ouroboros.Network.Magic (NetworkMagic (..))

data SyncEnv = SyncEnv
{ envBackend :: !SqlBackend
{ envPool :: !!Pool.Pool
, envCache :: !CacheStatus
, envConnectionString :: !ConnectionString
, envConsistentLevel :: !(StrictTVar IO ConsistentLevel)
Expand Down
6 changes: 3 additions & 3 deletions cardano-db-sync/src/Cardano/DbSync/Util/Constraint.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,9 +41,9 @@ dbConstraintNamesExists :: MonadIO m => SqlBackend -> m ManualDbConstraints
dbConstraintNamesExists sqlBackend = do
runReaderT queryRewardAndEpochStakeConstraints sqlBackend

queryIsJsonbInSchema :: MonadIO m => SqlBackend -> m Bool
queryIsJsonbInSchema sqlBackend = do
runReaderT DB.queryJsonbInSchemaExists sqlBackend
queryIsJsonbInSchema :: MonadIO m => Pool -> m Bool
queryIsJsonbInSchema pool = do
runReaderT DB.queryJsonbInSchemaExists pool

queryRewardAndEpochStakeConstraints ::
MonadIO m =>
Expand Down
1 change: 1 addition & 0 deletions cardano-db/cardano-db.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -89,6 +89,7 @@ library
, filepath
, file-embed
, hasql
, hasql-pool
, hasql-transaction
, iohk-monitoring
, lifted-base
Expand Down
6 changes: 3 additions & 3 deletions cardano-db/src/Cardano/Db/Error.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,15 +10,15 @@ module Cardano.Db.Error (
) where

import Cardano.BM.Trace (Trace, logError)
import Cardano.Db.Schema.Core
import Cardano.Db.Schema.Ids
import Cardano.Prelude (throwIO)
import Control.Exception (Exception)
import qualified Data.ByteString.Base16 as Base16
import Data.ByteString.Char8 (ByteString)
import Data.Text (Text)
import qualified Data.Text.Encoding as Text
import Data.Word (Word16, Word64)
import GHC.Generics (Generic)
import qualified Data.ByteString.Base16 as Base16
import qualified Data.Text.Encoding as Text

data LookupFail
= DbLookupBlockHash !ByteString
Expand Down
86 changes: 55 additions & 31 deletions cardano-db/src/Cardano/Db/PGConfig.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,48 +21,65 @@ import qualified Control.Exception as Exception
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as BS
import qualified Data.Text as Text
import Database.Persist.Postgresql (ConnectionString)
import System.Environment (lookupEnv, setEnv)
import System.Posix.User (getEffectiveUserName)
import qualified Hasql.Connection.Setting.Connection as HCS
import qualified Hasql.Connection.Setting.Connection.Param as HCSP
import qualified Hasql.Connection.Setting as HC
import Cardano.Prelude (decodeUtf8)
import Data.Word (Word16)
import qualified Data.Text.Read as Text (decimal)
import Control.Monad.Extra (unless)


data PGPassSource
= PGPassDefaultEnv
| PGPassEnv String
| PGPassCached PGConfig
deriving (Show)

-- | PGConfig as specified by https://www.postgresql.org/docs/11/libpq-pgpass.html
-- However, this module expects the config data to be on the first line.
-- | Preconstructed connection string according to <https://www.postgresql.org/docs/17/libpq-connect.html#LIBPQ-CONNSTRING the PostgreSQL format>.
data PGConfig = PGConfig
{ pgcHost :: ByteString
, pgcPort :: ByteString
, pgcDbname :: ByteString
, pgcUser :: ByteString
, pgcPassword :: ByteString
{ pgcHost :: Text.Text
, pgcPort :: Text.Text
, pgcDbname :: Text.Text
, pgcUser :: Text.Text
, pgcPassword :: Text.Text
}
deriving (Show)

newtype PGPassFile
= PGPassFile FilePath

toConnectionString :: PGConfig -> ConnectionString
toConnectionString pgc =
BS.concat
[ "host="
, pgcHost pgc
, " "
, "port="
, pgcPort pgc
, " "
, "user="
, pgcUser pgc
, " "
, "dbname="
, pgcDbname pgc
, " "
, "password="
, pgcPassword pgc
]
-- | Convert PGConfig to Hasql connection settings, or return an error message.
toConnectionString :: PGConfig -> Either String HC.Setting
toConnectionString pgc = do
-- Convert the port from Text to Word16
portWord16 <- textToWord16 (pgcPort pgc)
-- Build the connection settings
pure $ HC.connection (HCS.params [host, port portWord16 , user, dbname, password])
where
host = HCSP.host (pgcHost pgc)
port = HCSP.port
user = HCSP.user (pgcUser pgc)
dbname = HCSP.dbname (pgcDbname pgc)
password = HCSP.password (pgcPassword pgc)

-- | Convert a Text port to Word16, or return an error message.
textToWord16 :: Text.Text -> Either String Word16
textToWord16 portText =
case Text.decimal portText of
Left err ->
Left $ "Invalid port: '" <> Text.unpack portText <> "'. " <> err
Right (portInt, remainder) -> do
-- Check for leftover characters (e.g., "123abc" is invalid)
unless (Text.null remainder) $
Left $ "Invalid port: '" <> Text.unpack portText <> "'. Contains non-numeric characters."
-- Check if the port is within the valid Word16 range (0-65535)
unless (portInt >= (0 :: Integer) && portInt <= 65535) $
Left $ "Invalid port: '" <> Text.unpack portText <> "'. Port must be between 0 and 65535."
-- Convert to Word16
Right (fromIntegral portInt)

readPGPassDefault :: IO (Either PGPassError PGConfig)
readPGPassDefault = readPGPass PGPassDefaultEnv
Expand Down Expand Up @@ -94,24 +111,31 @@ readPGPassFile (PGPassFile fpath) = do
extract bs =
case BS.lines bs of
(b : _) -> parsePGConfig b
_ -> pure $ Left (FailedToParsePGPassConfig bs)
_otherwise -> pure $ Left (FailedToParsePGPassConfig bs)

parsePGConfig :: ByteString -> IO (Either PGPassError PGConfig)
parsePGConfig bs =
case BS.split ':' bs of
[h, pt, d, u, pwd] -> replaceUser (PGConfig h pt d u pwd)
_ -> pure $ Left (FailedToParsePGPassConfig bs)
[h, pt, d, u, pwd] ->
replaceUser (PGConfig
(decodeUtf8 h)
(decodeUtf8 pt)
(decodeUtf8 d)
(decodeUtf8 u)
(decodeUtf8 pwd)
)
_otherwise -> pure $ Left (FailedToParsePGPassConfig bs)
where
replaceUser :: PGConfig -> IO (Either PGPassError PGConfig)
replaceUser pgc
| pgcUser pgc /= "*" = pure $ Right pgc
| pgcUser pgc /= Text.pack "*" = pure $ Right pgc
| otherwise = do
euser <- Exception.try getEffectiveUserName
case euser of
Left (err :: IOException) ->
pure $ Left (UserFailed err)
Right user ->
pure $ Right (pgc {pgcUser = BS.pack user})
pure $ Right (pgc {pgcUser = Text.pack user})

-- | Read 'PGPassFile' into 'PGConfig'.
-- If it fails it will raise an error.
Expand Down
17 changes: 17 additions & 0 deletions cardano-db/src/Cardano/Db/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
{-# LANGUAGE OverloadedStrings #-}

module Cardano.Db.Run (
createPool,
getBackendGhci,
ghciDebugQuery,
runDbHandleLogger,
Expand Down Expand Up @@ -76,6 +77,22 @@ import Database.PostgreSQL.Simple (connectPostgreSQL)
import Language.Haskell.TH.Syntax (Loc)
import System.IO (Handle, stdout)
import System.Log.FastLogger (LogStr, fromLogStr)
import qualified Hasql.Pool as HP
import qualified Hasql.Pool.Config as HPC

-- | Create a connection pool.
createPool :: PGConfig -> IO HP.Pool
createPool pgc =
case toConnectionString pgc of
Left err -> error $ "createPool: " ++ err
Right connStr ->
HP.acquire $ HPC.settings
[ HPC.size 10 -- number of connections
, HPC.acquisitionTimeout 10 -- seconds
, HPC.agingTimeout 1800 -- 30 minutes
, HPC.idlenessTimeout 1800 -- 30 minutes
, HPC.staticConnectionSettings [connStr]
]

-- | Run a DB action logging via the provided Handle.
runDbHandleLogger :: Handle -> PGPassSource -> ReaderT SqlBackend (LoggingT IO) a -> IO a
Expand Down

0 comments on commit 53035ee

Please sign in to comment.