Skip to content

Commit 92ff532

Browse files
committed
update logs and correct pool_stat error
1 parent 6dfeb45 commit 92ff532

File tree

21 files changed

+501
-431
lines changed

21 files changed

+501
-431
lines changed

cardano-db-sync/src/Cardano/DbSync/Api.hs

Lines changed: 26 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,8 @@ module Cardano.DbSync.Api (
2828
getPruneConsume,
2929
getHasConsumedOrPruneTxOut,
3030
getSkipTxIn,
31+
initEpochStatistics,
32+
resetEpochStatistics,
3133
getPrunes,
3234
mkSyncEnvFromConfig,
3335
verifySnapshotPoint,
@@ -52,7 +54,7 @@ import Control.Concurrent.Class.MonadSTM.Strict (
5254
newTVarIO,
5355
readTVar,
5456
readTVarIO,
55-
writeTVar,
57+
writeTVar, StrictTVar,
5658
)
5759
import Control.Monad.Trans.Maybe (MaybeT (..))
5860
import qualified Data.Strict.Maybe as Strict
@@ -77,7 +79,7 @@ import qualified Ouroboros.Network.Point as Point
7779

7880
import qualified Cardano.Db as DB
7981
import Cardano.DbSync.Api.Types
80-
import Cardano.DbSync.Cache.Types (CacheCapacity (..), newEmptyCache, useNoCache)
82+
import Cardano.DbSync.Cache.Types (CacheCapacity (..), newEmptyCache, useNoCache, initCacheStatistics)
8183
import Cardano.DbSync.Config.Cardano
8284
import Cardano.DbSync.Config.Shelley
8385
import Cardano.DbSync.Config.Types
@@ -93,6 +95,7 @@ import Cardano.DbSync.Ledger.Types (HasLedgerEnv (..), LedgerStateFile (..), Sna
9395
import Cardano.DbSync.LocalStateQuery
9496
import Cardano.DbSync.Types
9597
import Cardano.DbSync.Util
98+
import qualified Data.Map.Strict as Map
9699

97100
setConsistentLevel :: SyncEnv -> ConsistentLevel -> IO ()
98101
setConsistentLevel env cst = do
@@ -392,6 +395,7 @@ mkSyncEnv trce dbEnv syncOptions protoInfo nw nwMagic systemStart syncNodeConfig
392395
oarq <- newTBQueueIO 1000
393396
epochVar <- newTVarIO initCurrentEpochNo
394397
epochSyncTime <- newTVarIO =<< getCurrentTime
398+
epochStatistics <- initEpochStatistics
395399
ledgerEnvType <-
396400
case (enpMaybeLedgerStateDir syncNP, hasLedger' syncNodeConfigFromFile) of
397401
(Just dir, True) ->
@@ -417,6 +421,7 @@ mkSyncEnv trce dbEnv syncOptions protoInfo nw nwMagic systemStart syncNodeConfig
417421
{ envDbEnv = dbEnv
418422
, envBootstrap = bootstrapVar
419423
, envCache = cache
424+
, envEpochStatistics = epochStatistics
420425
, envConsistentLevel = consistentLevelVar
421426
, envDbConstraints = dbCNamesVar
422427
, envCurrentEpochNo = epochVar
@@ -437,6 +442,25 @@ mkSyncEnv trce dbEnv syncOptions protoInfo nw nwMagic systemStart syncNodeConfig
437442
hasLedger' = hasLedger . sioLedger . dncInsertOptions
438443
isTxOutConsumedBootstrap' = isTxOutConsumedBootstrap . sioTxOut . dncInsertOptions
439444

445+
initEpochStatistics :: MonadIO m => m (StrictTVar IO EpochStatistics)
446+
initEpochStatistics = do
447+
curTime <- liftIO getCurrentTime
448+
liftIO $ newTVarIO $ EpochStatistics
449+
{ elsStartTime = curTime
450+
, elsCaches = initCacheStatistics
451+
, elsUnicodeNull = Map.empty
452+
}
453+
454+
resetEpochStatistics :: MonadIO m => SyncEnv -> m ()
455+
resetEpochStatistics syncEnv = liftIO $ do
456+
curTime <- getCurrentTime
457+
let newEpochStatsValue = EpochStatistics
458+
{ elsStartTime = curTime
459+
, elsCaches = initCacheStatistics
460+
, elsUnicodeNull = Map.empty
461+
}
462+
atomically $ writeTVar (envEpochStatistics syncEnv) newEpochStatsValue
463+
440464
-- | 'True' is for in memory points and 'False' for on disk
441465
getLatestPoints :: SyncEnv -> IO [(CardanoPoint, Bool)]
442466
getLatestPoints env = do

cardano-db-sync/src/Cardano/DbSync/Api/Ledger.hs

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -156,12 +156,10 @@ prepareTxOut ::
156156
prepareTxOut syncEnv (TxIn txIntxId (TxIx index), txOut) = do
157157
let txHashByteString = Generic.safeHashToByteString $ unTxId txIntxId
158158
let genTxOut = fromTxOut (fromIntegral index) txOut
159-
eTxId <- queryTxIdWithCache cache txIntxId
159+
eTxId <- queryTxIdWithCache syncEnv txIntxId
160160
txId <- case eTxId of
161161
Left err -> throwError err
162162
Right tid -> pure tid
163-
insertTxOut trce cache iopts (txId, txHashByteString) genTxOut
163+
insertTxOut syncEnv iopts (txId, txHashByteString) genTxOut
164164
where
165-
trce = getTrace syncEnv
166-
cache = envCache syncEnv
167165
iopts = soptInsertOptions $ envOptions syncEnv

cardano-db-sync/src/Cardano/DbSync/Api/Types.hs

Lines changed: 29 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
{-# LANGUAGE GADTs #-}
22
{-# LANGUAGE ScopedTypeVariables #-}
33
{-# LANGUAGE NoImplicitPrelude #-}
4+
{-# LANGUAGE OverloadedStrings #-}
45

56
module Cardano.DbSync.Api.Types (
67
SyncEnv (..),
@@ -10,6 +11,9 @@ module Cardano.DbSync.Api.Types (
1011
RunMigration,
1112
ConsistentLevel (..),
1213
CurrentEpochNo (..),
14+
UnicodeNullSource(..),
15+
EpochStatistics (..),
16+
formatUnicodeNullSource,
1317
) where
1418

1519
import Control.Concurrent.Class.MonadSTM.Strict (StrictTVar)
@@ -18,12 +22,13 @@ import qualified Data.Strict.Maybe as Strict
1822
import Data.Time.Clock (UTCTime)
1923
import Ouroboros.Consensus.BlockchainTime.WallClock.Types (SystemStart (..))
2024
import Ouroboros.Network.Magic (NetworkMagic (..))
25+
import qualified Data.Map.Strict as Map
2126

22-
import Cardano.Prelude (Bool, Eq, IO, Show, Word64)
27+
import Cardano.Prelude (Bool, Eq, IO, Show, Word64, Ord, Text)
2328
import Cardano.Slotting.Slot (EpochNo (..))
2429

2530
import qualified Cardano.Db as DB
26-
import Cardano.DbSync.Cache.Types (CacheStatus)
31+
import Cardano.DbSync.Cache.Types (CacheStatus, CacheStatistics)
2732
import Cardano.DbSync.Config.Types (SyncNodeConfig)
2833
import Cardano.DbSync.Ledger.Types (HasLedgerEnv)
2934
import Cardano.DbSync.LocalStateQuery (NoLedgerEnv)
@@ -38,6 +43,7 @@ import Cardano.DbSync.Types (
3843
data SyncEnv = SyncEnv
3944
{ envDbEnv :: !DB.DbEnv
4045
, envCache :: !CacheStatus
46+
, envEpochStatistics :: !(StrictTVar IO EpochStatistics)
4147
, envConsistentLevel :: !(StrictTVar IO ConsistentLevel)
4248
, envDbConstraints :: !(StrictTVar IO DB.ManualDbConstraints)
4349
, envCurrentEpochNo :: !(StrictTVar IO CurrentEpochNo)
@@ -98,3 +104,24 @@ data ConsistentLevel = Consistent | DBAheadOfLedger | Unchecked
98104
newtype CurrentEpochNo = CurrentEpochNo
99105
{ cenEpochNo :: Strict.Maybe EpochNo
100106
}
107+
108+
data UnicodeNullSource
109+
= InsertDatum
110+
| InsertRedeemerData
111+
| InsertScript
112+
| PrepareTxMetadata
113+
deriving (Eq, Ord, Show)
114+
115+
116+
formatUnicodeNullSource :: UnicodeNullSource -> Text
117+
formatUnicodeNullSource source = case source of
118+
InsertDatum -> "insertDatum: Column 'value' in table 'datum'"
119+
InsertRedeemerData -> "insertRedeemerData: Column 'value' in table 'redeemer'"
120+
InsertScript -> "insertScript: Column 'json' in table 'script'"
121+
PrepareTxMetadata -> "prepareTxMetadata: Column 'json' in table 'tx_metadata'"
122+
123+
data EpochStatistics = EpochStatistics
124+
{ elsStartTime :: !UTCTime
125+
, elsCaches :: !CacheStatistics
126+
, elsUnicodeNull :: !(Map.Map UnicodeNullSource [DB.TxId])
127+
}

0 commit comments

Comments
 (0)